perm filename INTOPS.OLD[OLD,HE] blob sn#500990 filedate 1980-03-24 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00002 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	.SBTTL	Table of interpreter instructions
C00022 ENDMK
C⊗;
.SBTTL	Table of interpreter instructions

COMMENT  ⊗
This table is parallel to the file INTDEF.SAI[AL,HE].  It is required
at several places in the interpreter; each of these can define the
macro MAKEOP however desired.  The convention here for types of
arguments that each pseudo-op takes is this:
	a	absolute address
	la	list of absolute addresses
	o	offset or level-offset pair
	lo	list of offsets or level-offset pairs
	n,t	small constants
	r50	word of radix 50
	r	used in POINTY, for relative address offset in words from curr
			position
⊗

PCVERSION == 9		;Fix this every time you add some new pcodes

	II == 2		;Start of interpreter jump table (0 is illegal instruction)

	;Motion control
MAKEOP	XMOVE,MOVE,<a,n,n,a,a>	;Prepare, execute move whose traj table is at a.
MAKEOP	XCENTER,CENTER,<a,n,n,a,a>, ;Center using traj table at a. Using mech n.
MAKEOP	XOPERATE,OPERATE,<n,n,n,n,a,a>,;Operate mech indicated by bits n,
			; some info on stack, operate started at A (for retry)
MAKEOP	XSTOP,STOP,<n>		;Cause mechanism n to stop.
MAKEOP	XTFRCST,TFRCST,<n>	;Initializes force system, force frame on stack
				; control bits in <n>
MAKEOP	XVMKFRC,VMKFRC	;Gets vector off stack, makes a force frame along vector
			; and puts it on the stack
MAKEOP	XCOMPLY,COMPLY,<n>	;Sets up compliant motion in next move
				;Gets force magnitude off stack, control bits in <n>
MAKEOP	XCMPOFF,CMPOFF,<n>	;Turns off compliant motion in current move (not used)
MAKEOP	XNOTICE,NOTICE		;Make sure everyone knows where the arm is.

	;Temp hacks for debugging force wrist
MAKEOP	XSETBAS,SETBAS		;Zero wrist callibration matrix
MAKEOP	XWRIST,WRIST,<o,o'>	;Store 6 force components in vectors o & o'
MAKEOP	XSTIFF,STIFF,<n>	;Sets stiffness (values on stack) for next move
MAKEOP	XGATHR,GATHR,<n>	;Tell arm code to gather force data on next move
MAKEOP	FILL2,NOOP		;filler
MAKEOP	FILL3,NOOP		;filler
MAKEOP	FILL4,NOOP		;filler

	;Variables
MAKEOP	XMVAR,MVAR,<<t,n,...>>	;Make n variables of type t with possible 
				;  optional arguments (list arg)
MAKEOP	XKVAR,KVAR,n		;Kill last n environment entries
MAKEOP	FILL5,NOOP		;filler
MAKEOP	FILL6,NOOP		;filler

	;Stack operations
MAKEOP	XGTVAL,GTVAL,<o>;Push value of arg (level-offset pair).
MAKEOP  XCHNGE,CHNGE,<o>;Pop value into arg (level-offset pair).
MAKEOP	XPUSH, PUSHV,<a> ;Push arg directly (as a ptr) onto stack. For cnstnts.

	;Flow of control
MAKEOP	XJUMP, JUMP, <a>	;Jump to address
MAKEOP	XJUMPC,JUMPC,<a>	;Jump to address if "true"
MAKEOP	XTERMINATE,TERMINATE	;Terminate this interpreter
MAKEOP  XPROC, PROC,<a,lo>	;Call a procedure at a, with arg list lo 
MAKEOP	XRETURN,RETURN,<n>	;Return from procedure
MAKEOP	XSPROUT,SPROUT,la	;Sprout interpreters at each arg, wait (list arg)
MAKEOP	XFORCHK,FORCHK,<o>,<a>	;Do a FOR-loop check, and fail to location d.
MAKEOP	XFOREND,FOREND,<a>	;Increment FOR variable and jump to FORCHK at a
MAKEOP	XCASE,CASE,<n,la>	;Does a regular case statement dispatch
MAKEOP	XSIGNAL,SIGNAL,<o>	;Signal event at level-offset o.
MAKEOP	XWAITE,WAITE,<o>	;Wait on event at level-offset o.
MAKEOP	XPAUSE,PAUSE		;Pause in seconds (on stack)
MAKEOP	XABORT,ABORT		;Abort current motions
MAKEOP	XDDT,GODDT		;go to DDT.
MAKEOP	FILL7,NOOP		;filler
MAKEOP	FILL8,NOOP		;filler
MAKEOP	FILL9,NOOP		;filler
MAKEOP	FILL10,NOOP		;filler
MAKEOP	FILL11,NOOP		;filler
MAKEOP	FILL12,NOOP		;filler

	;Affixment
MAKEOP	XAFFIX,AFFIX,<o,o',n (,o")>   ;Makes an affixement of type n between two
				;  frames at level-offsets o & o' (trans at o")
MAKEOP	XUNFIX,UNFIX,<o,o'>	;Unfixes the two frames at level-offsets: o & o"

	;Boolean
MAKEOP	XSLE,SLE	;S≤S  compare top two elts, pop, pop, push answer
MAKEOP	XSLT,SLT	;S<S		true := 1.0
MAKEOP	XSGE,SGE	;S≥S		false:=  0
MAKEOP	XSGT,SGT	;S>S
MAKEOP	XSEQ,SEQ	;S=S
MAKEOP	XSNE,SNE	;S≠S
MAKEOP	XAND,AND	;S∧S  (logical and)
MAKEOP	XLOR,LOR	;S∨S  (logical or)
MAKEOP	XNOT,NOT	;¬S   (logical not) note: this only takes one arg
MAKEOP	XXOR,LXOR	;S⊗S  (logical exclusive or)
MAKEOP	XEQV,EQV	;S≡S  (logical equivalence)
MAKEOP	FILL13,NOOP		;filler
MAKEOP	FILL14,NOOP		;filler

	;Arithmetic
MAKEOP	XWHERE,WHERE,<n>	;Push the current location of mechanism n
MAKEOP	XSADD, SADD	;S+S:  Add top two elts, pop, pop, push answer
MAKEOP	XSSUB, SSUB	;S-S:  Sub top two elts, pop, pop, push answer
MAKEOP	XSNEG, SNEG	;-S:   Negate top elt, pop, push answer
MAKEOP	XSMUL, SMUL	;S*S:  Mul top two elts, pop, pop, push answer
MAKEOP	XSDIV, SDIV	;S/S:  Div top two elts, pop, pop, push answer
MAKEOP	XSEXP,SEXP	;S↑S:  Raise scalar to a power
MAKEOP	XSABS,SABS	;|S|:  Absolute value of a scalar
MAKEOP	XINT,INT	;s ← INT s (integer part of)
MAKEOP	XIDIV,IDIV	;s ← INT(INT(s)/INT(s))
MAKEOP	XMOD,MOD	;s ← s MOD s
MAKEOP	XMAX,MAX	;s ← s MAX s
MAKEOP	XMIN,MIN	;s ← s MIN s
MAKEOP	XVMAGN, VMAGN	;S ← norm of vector
MAKEOP	XVDOT, VDOT	;S ← vector dot vector
MAKEOP	XSSBRTN,SSBRTN,<n>	;S ← SBRTN[n](top scalar elt)
MAKEOP	XTMAGN,TMAGN	;S ← extracts angle of rotation from trans
MAKEOP	XTAXIS,TAXIS	;V ← extracts axis of rotation from trans
MAKEOP	XVMAKE,VMAKE	;V ← vector(scalar,scalar,scalar)
MAKEOP	XSVMUL,SVMUL	;V ← scalar * vector
MAKEOP	XVSDIV,VSDIV	;V ← vector / scalar
MAKEOP	XVADD, VADD	;V ← vector + vector
MAKEOP	XVSUB, VSUB	;V ← vector - vector
MAKEOP	XUNITV,UNITV  	;Vector ← vector / its norm
MAKEOP  XVCROSS,CROSV	;Vector ← vector cross vector
MAKEOP	XTVMUL,TVMUL	;Vector ← trans * vector
MAKEOP	XTPOS,TPOS	;Vector ← translation_part_of_trans
MAKEOP	XTORIEN,TORIEN	;T ← rotation_part_of_trans
MAKEOP	XVSAXWR,VSAXWR	;T ← rotation(vector,angle)
MAKEOP	XTMAKE,TMAKE	;T ← trans(rot,vector)
MAKEOP	XTVADD,TVADD	;T ← t + v
MAKEOP	XTVSUB,TVSUB	;T ← t - v
	;FTOF		;T ← INV(t1) * t2  done by TTMUL(TINVRT(t1),t2) in pcode
MAKEOP	XTTMUL,TTMUL	;T ← trans * trans
MAKEOP	XTINVRT,TINVRT	;T ← inverse(trans)
MAKEOP	XCONSTR,CONSTR	;T ← construct(v,v,v)
MAKEOP	FILL15,NOOP		;filler
MAKEOP	FILL16,NOOP		;filler
MAKEOP	FILL17,NOOP		;filler
MAKEOP	FILL18,NOOP		;filler
MAKEOP	FILL19,NOOP		;filler

	;Condition monitors
MAKEOP	XCMENBL,CMENBL,<o>	;Enable c-m at level-offset o
MAKEOP	XCMDSBL,CMDSBL,<o>	;Disable c-m at level-offset o
MAKEOP	XCMTRIG,CMTRIG		;Trigger the c-m body (use only in checker)
MAKEOP	XCMSKED,CMSKED,<n>	;Sleep for n msecs (use only in checker)
MAKEOP	XCMUNCR,CMUNCR		;Start uncritical section
MAKEOP	XCMDONE,CMDONE 		;Ends force/hardware/duration c-m's, if c-m was
				; re-enabled then restarts it, else dismisses it
MAKEOP	XCMFORCE,CMFORCE	;Initialize force sensing - vector & level on stack
MAKEOP	XCMSENSE,CMSENSE	;Initialize hardware sensing
MAKEOP	XCMDUR,CMDUR		;Wait for set time, then start up c-m
MAKEOP	XCMWAIT,CMWAIT		;Special Wait for event cmon.
MAKEOP	FILL21,NOOP		;filler	(for hardware cmons?)
MAKEOP	FILL22,NOOP		;filler	(for hardware cmons?)
MAKEOP	FILL23,NOOP		;filler	(for hardware cmons?)
MAKEOP	FILL24,NOOP		;filler	(for hardware cmons?)

	;Initialization
MAKEOP	XPROG,PROG		;Initialize mechanism variables
MAKEOP	XENDP,ENDP		;Clean up mechanism variables

	;Input/Output
MAKEOP	XPROMPT,PROMPT	;Wait for a "P" on VT05 before proceeding
MAKEOP	XSCALRD,SCALRD	;Read in a scalar from the terminal
MAKEOP	XPRINT,PRINT	;Type an ASCIZ string on the VT05.
MAKEOP	XVALPRN,VALPRN	;Type a value, whatever type it is, and pop it.
MAKEOP	XVARPRN,VARPRN,<o>	;Type a variable (level-offset), whatever type.
MAKEOP	XQUERY,QUERY	;Read in a boolean from the VT05 - either "Y" or "N"
MAKEOP	FILL25,NOOP		;filler
MAKEOP	FILL26,NOOP		;filler
MAKEOP	FILL27,NOOP		;filler
MAKEOP	FILL28,NOOP		;filler
MAKEOP	FILL29,NOOP		;filler

	;Debugging aids
MAKEOP	XBREAK,BREAK	;Breakpoint in the program
MAKEOP	XNOOP,NOOP	;Null operation
MAKEOP	XTOPAL,TOPAL	;Escape to PAL

	;following added by MSM to get at new POINTY routines
	STSW	CPOINTY,0	; unless otherwise stated this is not a POINTY compilation
    .IFNZ CPOINTY
				; stack ops producing appropriate orientation
				; for the trans/frame on stack
MAKEOP	XUPARROW,UPARROW	; ↑ z-axis pointing upward
MAKEOP	XDOLLAR,DOLLAR		; $ station orientation, i.e. nilrot
MAKEOP	XALPHA,ALPHA		; α bgrasp orien at bpark, e.e. rot(zhat,180)
MAKEOP	XDWNARROW,DWNARROW	; ↓ bpark orien, i.e. rot(yhat,180)
MAKEOP	XEVAL,NOOP		;
MAKEOP	XWREAD,NOOP		; Wrist reading routine
MAKEOP  XPUSHSCI, PUSHSCI 	; Push floating point scalar immediate
MAKEOP	XPUSHINTI, PUSHINTI,<n>	; like pushsci but argument is an integer
MAKEOP	XAGTVAL, AGTVAL,<n,o>	; like gtval except pushes array value 
MAKEOP	XACHNGE, ACHNGE,<n,o>
MAKEOP	XRTVAL, RTVAL,<o>	; returns value of levof in return buffer
MAKEOP	XARTVAL, ARTVAL,<n,o>	; like rtval, only for array
MAKEOP	XSPLUS,NOOP		; dummy
MAKEOP	XVPLUS,NOOP		; dummy
MAKEOP	XVNEG,VNEG		; take negative of the top element which is a vector
MAKEOP	XVSMUL,VSMUL		; intert top two arguments and call svmul
MAKEOP	XWRT,WRT		; v wrt t = orient(t)*v
MAKEOP	XVFREL,VFREL		; v rel f = t*v
MAKEOP	XFTOF,FTOF		;t1→t2 = inv(t1)*t2
MAKEOP	XFFREL,FFREL		; f rel t = t*f
MAKEOP	XFCONSTR,FCONSTR	; like constr, but takes three frames instead
MAKEOP	XATAN2,PATAN2
MAKEOP	XPDONE,PDONE		; use instead of terminate
MAKEOP	XGTBLK,GTBLK,<n,<t>,r>
MAKEOP	XRJMP,RJMP,<r>		; like JUMP but relative offset
MAKEOP	XRJMPC,RJMPC,<r>	; like JUMPC but relative offset
MAKEOP	XSTIF0,STIF0		; does default setstiff
MAKEOP	XRPMOVE,RPMOVE,<r,n>	; pointy move
MAKEOP	XRTADRIVE,RTADRIVE,<r,n>	; abs drive
MAKEOP	XRTDDRIVE,RTDDRIVE,<r,n>	; rel drive
MAKEOP	XRCENTER,RCENTER,<r,n>	;center
MAKEOP	XGATHER,GATHER,<n,n>	;turn data gather on
MAKEOP	XRFORCE,RFORCE		;gather raw force data
MAKEOP	XDISVT05,DISVT05,<n>	;turn on and off the joint angle display
MAKEOP	XAPUSHOFFSET,APUSHOFFSET,<n,n>	; push index and offset onto stack
MAKEOP	XPUSHOFFSET,PUSHINTI,<n>	; push offset onto stack
MAKEOP	XGTINT,GTINT		;Get value of top element of stack (integer off)
MAKEOP	XGVALS,GVALS		; get the value of variable whose offset is on stack
MAKEOP	XCHNGS,CHNGS		; change the value of the variable whose offset is on stack
MAKEOP	XPAFFIX,PAFFIX		; affix elements found on stack, and return arguments
MAKEOP	XPUNFIX,PUNFIX		; unfix elements found on stack, and return argumentss
MAKEOP	XSETSTF,SETSTF		; takes the twelve scalars on stack and jumps to arm code
MAKEOP	XRTARR,RTARR,<o>	; returns values in the array
MAKEOP	XRTPARS,RTPARS,<o>	; returns parameters of the array
MAKEOP	XPRVAL,PRVAL,<n>	; prints value on stack according to type <n>
MAKEOP	XARRINI,ARRINI,<o>	; initializes array with offset o
MAKEOP	XPSPROUT,PSPROUT	; position indep version of SPROUT
MAKEOP	XCHCMP,CHCMP,<n>		; change value of trans/vector coord 1,2,3
MAKEOP	XCHTPOS,CHTPOS			; change pos of trans
MAKEOP  XCHTORIENT,CHTORIENT		; change orient of trans
MAKEOP	XRCASE,RCASE			; case instruction of POINTY
MAKEOP	XPSIGNAL,PSIGNAL		; SIGNAL instruction of POINTY
MAKEOP	XPWAIT,PWAIT		; WAIT(E !) instruction of POINTY
MAKEOP	XPRNTI,PRINTI		; print string following immediately
MAKEOP	XPRNTC,PRINTC		; print character following immediately
MAKEOP	XMKVT,MKVT		; make a vector out of following 3 fp nums
MAKEOP	XMKRT,MKRT		; make trans out of following 3 fp nums in euler rep
MAKEOP	XMKTR,MKTR		; make trans out of following 6 fp nums in euler rep
MAKEOP	XARRLD,ARRLD,<o,n>	; load array o type n with following elements
MAKEOP	XRFRCHK,RFRCHK		; FORCHK equivalent of AL
MAKEOP	XRFOREND,RFOREND	; FOREND equivalent of AL
MAKEOP	XPWRIST,PWRIST		; POINTY version of wrist
MAKEOP	XPUSHPC,PUSHPC		; push ipc onto interpreter stack for use with PRETRY
MAKEOP	XPRETRY,PRETRY		; AL source code RETRY
MAKEOP	XMDONE,MDONE		; cleanup R3 stack from the PUSHPC
MAKEOP	XPCMWAIT,PCMWAIT	; CMWAIT, but argument on the stack
MAKEOP	XSETSPEED,SETSPEED	; set speed_factor
MAKEOP	XGTCMP,GTCMP,<n>	; get vector component n=0 for x,4 for y,8 for z
MAKEOP	XTVREL,TVREL		; computes t + v wrt t
MAKEOP	XCMVAR,CMVAR,<n>	; makes n cmons without bodies
MAKEOP	XCMFIL,CMFIL,<o>	; fill in body of condition monitor
MAKEOP	XPKVAR,PKVAR,<n>	; calls kvar is n>0 else returns
MAKEOP	XPOPERATE,POPERATE	; set up for OPERATE to call
    .ENDC